home *** CD-ROM | disk | FTP | other *** search
/ SGI Hot Mix 17 / Hot Mix 17.iso / HM17_SGI / research / lib / slicer.pro < prev    next >
Text File  |  1997-07-08  |  54KB  |  1,718 lines

  1. ; $Id: slicer.pro,v 1.25 1997/02/13 00:00:04 ali Exp $
  2. ;
  3. ; Copyright (c) 1991-1997, Research Systems, Inc.  All rights reserved.
  4. ;       Unauthorized reproduction prohibited.
  5.  
  6. ;
  7. ; Conventions:
  8. ; Faces = faces of cube.  Numbered 0 to 5:
  9. ;        0 = X = c0[0]  (Corner 0)
  10. ;        1 = Y = c0[1]
  11. ;        2 = Z = c0[2]
  12. ;        3 = X = c1[0]  (Corner 1)
  13. ;        4 = Y = c1[1]
  14. ;        5 = Z = c1[2]
  15. ; Orientations:
  16. ;    6 = reset to default.
  17. ;    0 = xy exchange, 1 = xz exchange, 2 = yz exchange.
  18. ;    3 = x reverse, 4 = y reverse, 5 = z reverse.
  19. ; Vertex indices:    Faces
  20. ;    0    0,0,0   0,1,2
  21. ;    1    N,0,0    1,2,3
  22. ;    2    0,N,0    0,2,4
  23. ;    3    N,N,0    2,3,4
  24. ;    4    0,0,N    0,1,5
  25. ;    5    N,0,N    1,3,5
  26. ;    6    0,N,N    0,4,5
  27. ;    7    N,N,N    3,4,5
  28. ;
  29. ; Edge Index    Vertex Indices
  30. ;    0    0-1
  31. ;    1    1-2
  32. ;    2    2-3
  33. ;    3    3-1
  34. ;    4    0-4
  35. ;    5    1-5
  36. ;    6    2-6
  37. ;    7    3-7
  38. ;    8    4-5
  39. ;    9    5-6
  40. ;    10    6-7
  41. ;    11    7-4
  42. ;
  43. ; Modes:
  44. ;    0 = Slices
  45. ;    1 = Cube
  46. ;    2 = Cut
  47. ;    3 = Isosurface
  48. ;    4 = Probe
  49. ;    5 = rotations
  50.  
  51.  
  52. function p_inside_poly, polyv, p
  53. ;    polyv = [2,n] array of polygon vertices, either clockwise or
  54. ;        counter-clockwise order.  Polygon must be convex.
  55. ;    p = (2) point coordinates.
  56. ;    return 0 if point is outside polygon, 1 if inside.
  57. ;
  58. x = float(p[0])
  59. y = float(p[1])
  60. np = n_elements(polyv)/2        ;# of vertices
  61. x1 = polyv[0,np-1]        ;Start at last point
  62. y1 = polyv[1,np-1]
  63.  
  64. pos = -1
  65. for i=0,np-1 do BEGIN
  66.     x2 = polyv[0,i]
  67.     y2 = polyv[1,i]
  68.     k = (x*(y1-y2) + y * (x2-x1) + x1*y2-y1*x2)  ;Side of line point is on
  69.     if k eq 0 THEN BEGIN    ;On line?
  70.         if (y lt (y1< y2)) or (y gt (y1 > y2)) or  $  ;Check more
  71.         (x lt (x1 < x2)) or (x gt (x1 > x2)) THEN return,0
  72.     ENDIF ELSE BEGIN        ;Not on line
  73.         k = k gt 0        ;1 if on right side
  74.         if pos lt 0 then pos = k
  75.         if pos ne k THEN return,0
  76.     ENDELSE
  77.     x1=x2        ;Previous vertex
  78.     y1=y2
  79.     ENDFOR
  80. return,1
  81. end
  82.  
  83.  
  84.  
  85. Function p_inverse, x, y, z
  86. ;
  87. ; Given one or more screen coordinates, and their Z-buffer values
  88. ; return the object space (volume subscript) coordinates of that point.
  89. ;
  90. ;  On input: x, y = scalars or vectors containing the device coordinate(s)
  91. ;    z = zbuffer value(s) at [x,y]
  92. ;  Result: [3,n] vector of object space (volume) coordinates.
  93.  
  94. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  95.  
  96. ; Method:
  97. ; - Convert screen coords to normalized coords.
  98. ; - Multiply by inverse of 3D transformation.
  99. ; - Scale back to data coordinates.
  100. ;
  101. ; ******* Old way *************
  102. ; ones = replicate(1, n_elements(x))
  103. ; v = [[x /  float(!d.x_size)], $        ;To normalized coordinates.
  104. ;      [y / float(!d.y_size)], $
  105. ;      [z/65530.+0.5], $
  106. ;      [ones]]
  107. ; v = ((temporary(v) # sl.pt_inverse) - (ones # [!x.s[0], !y.s[0], !z.s[0]])) / $
  108. ;     (ones # [ !x.s[1], !y.s[1], !z.s[1]])
  109. ;
  110. ; **************************
  111. ; The new way folds everything into the matrix multiplication operation
  112. ; and is much faster, although its very, very, obtuse.
  113.  
  114. ; Apply to normalized conversion to inverse matrix.
  115. q = sl.pt_inverse * (1./[!d.x_size, !d.y_size, 65530., 1.]  # replicate(1.,4))
  116.  
  117. s = 1./[!x.s[1], !y.s[1], !z.s[1], 1.0]   ;To data coord scale factors
  118. t = [!x.s[0], !y.s[0], !z.s[0], 0.0]
  119. q = q * transpose(s # replicate(1.,4)) ; Mult inv matrix by 1/![xyz].s[1]
  120. q[3,0] = q[3,*] - transpose(t * s)    ;Add in t*s.
  121. return, ([[x],[y],[z+32765L], [replicate(1L, n_elements(x))]] # q)[*,0:2]
  122. end
  123.  
  124.  
  125.  
  126. Function slicer_plane_int, dummy
  127. ; Return the intersections of the plane with the volume cube.
  128. ; V[3,12] = intersections of plane with the 12 edges.
  129. ; Flags[12] = 1 if there is an intersection at that edge.
  130. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  131.  
  132. Jn = sl.orthop[0:2]            ;Plane eqn
  133. Jd = sl.orthop[3]
  134.  
  135. v = fltarr(3,12)
  136. k = 0
  137.  
  138. for i=0,11 do begin            ;Faces
  139.     p0 = sl.p0[*,sl.edges[0,i]]        ;Beginning of edge
  140.     p1 = sl.p0[*,sl.edges[1,i]]        ;End of edge
  141.     lv = p1-p0
  142.     t = total(lv * Jn)
  143.     if t ne 0 then begin
  144.     t = -(jd + total(p0 * Jn)) / t
  145.     p = p0 + t * lv            ;Point of intersection
  146.     d = min((p - p0) * (p1-p))
  147.     if d ge 0.0 then begin        ;Within edge?
  148.         v[0,k] = p            ;Yes, save intersection
  149.         k = k + 1
  150.         endif          
  151.     endif                ;T ne 0
  152.     endfor                    ;i
  153.  
  154. ; Sort into order:
  155. d = max(abs(Jn), m)            ;Largest plane coeff = what we ignore
  156. u = v[[m+1, m+2] mod 3, 0:k-1]        ;Get other 2 coords
  157. a = fltarr(k)                ;Angle measure
  158. d = min(u[1,*], dmin)            ;Get lowest point
  159. u_dx = u[0,*]-u[0,dmin]
  160. u_dy = u[1,*]-u[1,dmin]
  161. zero_ind = Where((u_dx EQ 0.0) AND (u_dy EQ 0.0))
  162. if (zero_ind[0] GE 0L) THEN u_dx[zero_ind] = 1.0
  163. a=atan(u_dy, u_dx)
  164. zero_ind=0 & u_dx=0 & u_dy=0
  165. a[dmin] = -100.                ;Anchor = first
  166. n = sort(a)                ;Go around anchor point & back
  167. return, v[*, [n, n[0]]]
  168. end
  169.  
  170.  
  171.  
  172.  
  173. PRO SLICER_PLAYBACK, FILE = file, Commands
  174. ; Play back a journal.  Commands are either in the designated file
  175. ; or in the string array Commands".
  176. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  177. COMMON slicer_common1, old_slice, d0, z0, az, el
  178.  
  179. if n_elements(file) gt 0 THEN BEGIN    ;Read from file
  180.     OPENR, unit, /GET_LUN, file, ERROR = i
  181.     if i ne 0 then begin    ;OK?
  182.         widget_control, sl.file_text[1], set_value = !ERR_STRING
  183.         return
  184.         ENDIF
  185.     commands = strarr(100)        ;Read up to 100 lines
  186.     i = 0
  187.     a = ''
  188.     while not eof(unit) do begin
  189.         readf, unit, a
  190.         commands[i] = a
  191.         i = i + 1
  192.         endwhile
  193.     ncommands = i
  194.     free_lun, unit
  195. ENDIF ELSE ncommands = n_elements(commands)
  196.  
  197. IF mode ne 7 THEN BEGIN            ;Not our mode?
  198.     if sl.mode_bases[mode] ne 0 THEN $  ;Remove panel if mapped
  199.         WIDGET_CONTROL, sl.mode_bases[mode], MAP=0
  200.     mode = 7            ;New mode = ours
  201.     WIDGET_CONTROL, sl.mode_bases[mode], MAP=1
  202.     ENDIF
  203.  
  204. pars = fltarr(10)
  205.  
  206. for i=0, ncommands-1 do begin        ;Each command
  207.     s = strtrim(strcompress(commands[i]))    ;Parse it, extracting fields
  208.     j = 0
  209.     m = 0
  210.     while j lt strlen(s) do begin    ;While string left
  211.         k = strpos(s, ' ', j)    ;Find next blank
  212.         if k le 0 then k = strlen(s)  ;if none, go to end of string
  213.         if j eq 0 then cmd = strmid(s,0,k) $
  214.         else begin pars[m] = strmid(s,j,k) & m=m+1 & endelse
  215.         j = k+1
  216.         endwhile
  217.     WIDGET_CONTROL, sl.file_text[1], SET_VALUE = strmid(s,0,32)
  218.     case strupcase(cmd) of        ;Interpret commands.....
  219. "UNDO": slicer_undo
  220. "ORI":  BEGIN    ;AXIS(3), AXIS_REVERSE(3), ROTATIONS(2)
  221.     sl.axex = pars[0:2]
  222.     sl.axrev = pars[3:5]
  223.     sl.rotation = pars[6:7]
  224.     for j=0,1 do WIDGET_CONTROL, sl.rslide[j], SET_VALUE = sl.rotation[j]
  225.     WIDGET_CONTROL, sl.rslide[2], SET_VALUE=string(pars[8])  ;Aspect
  226.     SLICER_ORIENTATION
  227.     ENDCASE
  228. "TRANS": BEGIN   ;On/Off Threshold(%)
  229.     sl.trans = pars[0]
  230.     if sl.trans eq 0 then pars[1] = 100
  231.     sl.threshold = pars[1] /100. * sl.nc3
  232.     WIDGET_CONTROL, sl.threshold_slider, SET_VALUE = pars[1]
  233.     ENDCASE
  234. "SLICE": BEGIN      ;Axis, slice_value, interp, expose, 0 for orthogonal
  235.         ;Azimuth, Elev, interp, expose, 1, x0, y0, z0 for oblique
  236.     sl.interp = pars[2]
  237.     sl.expose = pars[3]
  238.     if pars[4] eq 0 then begin    ;Orthogonal slices?
  239.         WIDGET_CONTROL, sl.draw_butt[sl.expose], /SET_BUTTON
  240.         SLICER_DRAW, pars[0], pars[1]
  241.     ENDIF ELSE BEGIN        ;Oblique slice
  242.         az = pars[0]
  243.         el = pars[1]
  244.         s = sin(el * !DTOR)
  245.         sl.orthop[0] = sin(-az * !dtor) * s
  246.         sl.orthop[1] = cos(-az * !dtor) * s
  247.         sl.orthop[2] = cos(el * !dtor)
  248.         z0 = pars[5:7]
  249.         sl.orthop[3] = -total(sl.orthop * z0)
  250.         d0 = slicer_plane_int()
  251.         slicer_oblique
  252.     ENDELSE
  253.     ENDCASE
  254. "COLOR": BEGIN     ;Table_num (-1 = present), low, high, shading
  255.     sl.stretch = pars[1:2]
  256.     sl.shading = pars[3]/100.
  257.     for j=0,2 do WIDGET_CONTROL, sl.cslide[j], SET_VALUE = pars[j+1]
  258.     slicer_colors,     pars[0]
  259.     ENDCASE
  260. "ISO":  BEGIN        ;value, hi/lo
  261.     sl.isop.value = pars[0] / 100. * (sl.amax-sl.amin) + sl.amin
  262.     sl.isop.hi_lo = pars[1]
  263.     DO_ISOSURFACE
  264.     ENDCASE
  265. "ERASE":  slicer_erase
  266. "WAIT":  wait, pars[0]
  267. "CUBE": BEGIN        ;mode (1 = block, 0 = cutout), cut_ovr, interp,
  268.             ; start_coords(3), end_coords(3)
  269.     mode = pars[0]
  270.     sl.cut_ovr = pars[1]
  271.     sl.interp = pars[2]
  272.     sl.p0cube = reform(pars[3:8], 3,2)
  273.     DO_CUBE    
  274.     ENDCASE
  275.     ENDCASE
  276.   ENDFOR
  277. mode=7
  278. WIDGET_CONTROL, sl.file_text[1], SET_VALUE = 'Playback Done'
  279. end
  280.  
  281. ; Journal events if journal file is open.
  282. PRO SLICER_JOURNAL, name, params
  283. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  284.  
  285. if sl.journal le 0 then return
  286. if n_elements(params) le 0 then params = 0.
  287. printf, sl.journal, name, params, format='(A, 1x, 10F10.3)'
  288. end
  289.  
  290.  
  291. PRO SLICER_UNDO        ;Undo last operation
  292. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  293.  
  294. SLICER_JOURNAL, "UNDO"
  295. if n_elements(zb_last) le 1 then return
  296. set_plot,'Z'
  297. tmp = tvrd(/WORDS, CHANNEL=1)  ;Read depth buffer & swap
  298. tv, zb_last, CHANNEL=1, /WORDS
  299. zb_last = temporary(tmp)
  300. tmp = tvrd()        ;Swap them
  301. tv, z_last
  302. slicer_show, z_last
  303. z_last = tmp
  304. end
  305.  
  306.  
  307. PRO slicer_orientation, i    ;i = orientation
  308. ;  Set the New Orientation
  309. COMMON volume_data, a
  310. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  311. if n_elements(i) gt 0 THEN BEGIN
  312.     if i le 2 THEN BEGIN
  313.         j = 2 * i
  314.         ll = ([0,1,0,2,1,2])[j:j+1]  ;axes to swap
  315.         t = sl.axex[ll[0]] & sl.axex[ll[0]] = sl.axex[ll[1]] & 
  316.         sl.axex[ll[1]] = t
  317.     ENDIF ELSE if i eq 6 THEN BEGIN
  318.         sl.axex = [0,1,2]        ;default transformation
  319.         sl.axrev = intarr(3)
  320.     ENDIF ELSE sl.axrev[i-3] = 1-sl.axrev[i-3]  ;reverse
  321. ENDIF        
  322.  
  323. d = [ 0., dims[0], 0., dims[1], 0., dims[2]]
  324. f = 1.0
  325. WIDGET_CONTROL, sl.rslide[2], GET_VALUE=s
  326. ON_IOERROR, bad_aspect
  327. f = (float(s))[0]
  328. if (f le 0.0) then goto, bad_aspect
  329. IF f gt 1. THEN BEGIN
  330.     x = (f-1)/2.
  331.     d[0] = [-x * dims[0], (x+1) * dims[0], -x * dims[1], (x+1) * dims[1]]
  332. ENDIF ELSE BEGIN
  333.     x = (1-f)/2
  334.     d[4] = [-x * dims[2], (x+1) * dims[2]]
  335. ENDELSE
  336. bad_aspect:
  337. SLICER_JOURNAL, "ORI", [sl.axex, sl.axrev, sl.rotation, f ]
  338.  
  339. for i=0,2 do if sl.axrev[i] THEN BEGIN    ;Swap endpoints for reversed axes
  340.     j=i*2
  341.     t = d[j] & d[j] = d[j+1] & d[j+1] = t
  342.     ENDIF
  343.  
  344. !x.type = 0        ;make sure its linear
  345. scale3, xrange=d[0:1], yrange=d[2:3], zrange=d[4:5], ax = sl.rotation[0], $
  346.     az = sl.rotation[1]
  347.  
  348. k = 1        ;current y axis
  349. if sl.axex[0] ne 0 THEN BEGIN    ;swap x?
  350.     if sl.axex[0] eq 1 THEN BEGIN &    t3d, /XYEXCH & k = 0
  351.     ENDIF ELSE t3d,/XZEXCH
  352. ENDIF
  353.  
  354. if k ne sl.axex[1] THEN t3d,/YZEXCH
  355. slicer_erase
  356. if mode le 2 THEN draw_orientation
  357. sl.pt_inverse = invert(!p.t)
  358. end
  359.  
  360.  
  361.  
  362.  
  363.  
  364. PRO slicer_oblique        ;Do an oblique slice
  365. ;    Plane eqn is in sl.orthop
  366. ;    d0 is the intersections of the plane with the edges of the volume
  367. ;        cube.
  368. COMMON volume_data, a
  369. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  370. COMMON slicer_common1, old_slice, d0, z0, az, el
  371.  
  372. if n_elements(d0) le 3 then return        ;Anything?
  373.  
  374. SLICER_JOURNAL, "TRANS", [sl.trans, sl.threshold * 100. / sl.nc3]
  375. SLICER_JOURNAL, "SLICE", [az, el, sl.interp, sl.expose, 1., z0 ]
  376.  
  377. widget_control, sl.pos_text, set_value = 'Extracting Oblique Slice'
  378. set_plot,'Z'
  379. z = (z_last = tvrd())            ;save previous image & z
  380. zb = (zb_last = tvrd(CHANNEL=1, /WORDS))
  381. erase
  382. polyfill, d0, /T3D, /DATA    ;Mark the slice
  383. z1 = tvrd(CHANNEL=1, /WORDS)    ;Read depth buffer
  384.  
  385. if sl.expose then points = where((z1 lt zb_last) and (z1 ne z1[0,0])) $
  386.     else points = where(z1 gt zb_last)
  387.  
  388. if points[0] lt 0 then begin
  389.     z=z_last
  390.     zb = zb_last
  391.     goto, done
  392.     endif
  393.  
  394. widget_control, sl.pos_text, set_value = $
  395.     STRING(n_elements(points), FORMAT="(i6, ' points')")
  396.  
  397. ; Get voxel subscripts from screen coords:
  398. v = p_inverse(points mod !d.x_size, points / !d.x_size, z1[points])
  399.  
  400. ;        Either interpolate or pick nearest neighbor
  401. if sl.interp THEN v = interpolate(a, v[*,0], v[*,1], v[*,2]) $
  402.     else v = a[long(temporary(v)) # [1, dims[0], dims[0] * dims[1]]]
  403.  
  404. v = bytscl(temporary(v), max=sl.amax, min=sl.amin, top = sl.nc3-1) ;face data
  405.  
  406. if sl.trans THEN BEGIN        ;Transparency?  Remove those under thresh.
  407.     good = where(v ge sl.threshold)
  408.     v = v[good]
  409.     points = points[good]
  410.     endif
  411.  
  412. dummy = max(abs(sl.orthop[0:2]), kmax)    ;Axis with smallest variation
  413. if kmax ne 0 then z[points] = v + byte(kmax * sl.nc3)  $ ;Shade it
  414. else z[points] = v
  415.  
  416. zb[points] = z1[points]        ;Update depth buffer
  417.  
  418. done: tv, z                    ;Now show it
  419. tv, zb, /WORDS, CHANNEL=1        ;and update depth buffer
  420.  
  421. widget_control, sl.pos_text, set_value = $
  422.       STRING(z0, az, el, FORMAT="('(',3f5.1,') A=', i4, ' E=',i4)")
  423. slicer_show
  424. end
  425.  
  426.  
  427.  
  428.  
  429. PRO slicer_draw, ax, slice        ;draw a slice.
  430. ;  ax = axis, 0 for x, 1 for Y, 2 for Z. slice = plane number.
  431. COMMON volume_data, a
  432. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  433.  
  434. WIDGET_CONTROL, sl.base, /HOURGLASS
  435. SLICER_JOURNAL, "TRANS", [sl.trans, sl.threshold * 100. / sl.nc3]
  436. SLICER_JOURNAL, "SLICE", [ax, slice, sl.interp, sl.expose, 0.]
  437.  
  438. set_plot,'Z'
  439. z_last = tvrd()            ;save previous image & z
  440. zb_last = tvrd(CHANNEL=1, /WORDS)
  441.  
  442. d0 = [0,0,0]
  443. d1 = dims -1
  444. d0[ax] = slice
  445. d1[ax] = slice
  446.  
  447. if sl.expose THEN erase        ;Get a clean slice
  448.                 ;extract & scale the slice
  449. offset = byte(ax*sl.nc3)    ;bias for this slice
  450. p = bytscl(a[d0[0]:d1[0], d0[1]:d1[1], d0[2]:d1[2]], $
  451.     max=sl.amax, min=sl.amin, top = sl.nc3-1)
  452.  
  453. if sl.trans THEN t = (sl.threshold > 1) + offset $  ;lower limit
  454.     ELSE t = 0
  455. if ax ne 0 THEN p = p + offset    ;add bias
  456. d1 = dims-1
  457. s = replicate(slice, 4)
  458.  
  459. case ax of
  460. 0:    polyfill, s, [0,d1[1],d1[1],0],[0,0,d1[2],d1[2]],/T3D,$
  461.         pat=reform(p, dims[1], dims[2], /OVER), $
  462.         image_coord = [0,0, d1[1],0, d1[1],d1[2], 0,d1[2]], $
  463.         image_interp= sl.interp, trans=t
  464. 1:    polyfill, [0,d1[0],d1[0],0],s,[0,0,d1[2],d1[2]],/T3D,$
  465.         pat=reform(p, dims[0], dims[2], /OVER), $
  466.         image_coord = [0,0, d1[0],0, d1[0],d1[2], 0,d1[2]], $
  467.         image_interp= sl.interp, trans=t
  468. 2:    polyfill,[0,d1[0],d1[0],0],[0,0,d1[1],d1[1]],s,/T3D,$
  469.         pat=reform(p, dims[0], dims[1], /OVER),$
  470.         image_coord = [0,0, d1[0],0, d1[0],d1[1], 0,d1[1]], $
  471.         image_interp= sl.interp, trans=t
  472.     ENDCASE
  473.  
  474. if sl.expose THEN BEGIN
  475.     z = tvrd(/WORDS, CHANNEL=1)    ;The new slice
  476.     pnts = where((z gt zb_last) + (z eq z[0,0])) ;where we display prev
  477.     if n_elements(pnts) gt 1 then begin
  478.         z[pnts] = zb_last[pnts]        ;New Z
  479.         tv, z, /WORDS, CHANNEL=1
  480.         z = tvrd()            ;New display
  481.         z[pnts] = z_last[pnts]
  482.         tv, z
  483.         ENDIF
  484.     ENDIF
  485. slicer_show
  486. end
  487.  
  488. PRO slicer_colors, table    ;load our color table
  489. ; Table = index of color table to load, -1 to retain present.
  490. ; The color palette is repeated 3 times, once for each of the possible face
  491. ; directions.  The colors indices:
  492. ;  3 * sl.nc3  = red
  493. ;  3 * sl.nc3 + 1 = green
  494. ;  3 * sl.nc3 + 2 = blue
  495. ;  3 * sl.nc3 + 3 = white
  496.  
  497. COMMON volume_data, a
  498. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  499. common colors, r_orig, g_orig, b_orig, r_curr, g_curr, b_curr
  500.  
  501. v = [0, .5, 1.]        ;Shading of the planes.
  502. if n_params() eq 0 then table = -1
  503. if table ge 0 then loadct, /SILENT, table
  504. SLICER_JOURNAL, "COLOR", [table, sl.stretch, 100. * sl.shading]
  505.  
  506. t = sl.stretch /100. * sl.nc3
  507. if t[1] eq t[0] then s = sl.nc3 else s = sl.nc3 / (t[1]-t[0])
  508. q = long(3*s*(findgen(sl.nc3) - t[0]))
  509.  
  510.  
  511. r_curr = bytarr(3*sl.nc3)
  512. g_curr = r_curr
  513. b_curr = r_curr
  514. s = 1.-sl.shading
  515. for i=0,2 do begin        ;3 faces
  516.     v0 = sl.shading * v[i] * 255
  517.     r_curr[i*sl.nc3] = s * r_orig[q] + v0
  518.     g_curr[i*sl.nc3] = s * g_orig[q] + v0
  519.     b_curr[i*sl.nc3] = s * b_orig[q] + v0
  520.     endfor
  521. tvlct, r_curr, g_curr, b_curr
  522.     ; load last 4 colors as red, green, blue, white
  523. tvlct, [255,0,0,255],[0,255,0,255],[0,0,255,255],3*sl.nc3
  524. end
  525.  
  526. PRO DO_ISOSURFACE        ;Draw the isosurface
  527. COMMON volume_data, a
  528. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  529.  
  530.  
  531. WIDGET_CONTROL, sl.base, /HOURGLASS
  532. SLICER_JOURNAL, "ISO", [(sl.isop.value-sl.amin)/(sl.amax-sl.amin)*100, $
  533.         sl.isop.hi_lo]
  534. set_plot,'Z'
  535. widget_control, sl.pos_text, set_value='Computing Polygons'
  536. shade_volume, a, sl.isop.value, verts, polys, $
  537.     low = sl.isop.hi_lo
  538. if n_elements(verts) eq 0 then begin
  539.     widget_control, sl.pos_text, set_value = $
  540.     'No surface at this value'
  541.     set_plot,sl.gdev
  542. endif else begin
  543.   widget_control, sl.pos_text, set_value = $
  544.     strtrim((size(verts))[2],2)+' Vertices, ' + $
  545.     strtrim((size(polys))[1]/4,2) + ' Polygons.'
  546.   z_last = tvrd()            ;Save old display
  547.   zb_last = tvrd(CHANNEL=1, /WORDS)
  548.   SET_SHADING, Values=[0, sl.nc3-1]
  549.   b = polyshade(verts,polys,/T3D,top=sl.nc3-1)
  550.   verts = 0 & polys = 0        ;Free space
  551.   slicer_show
  552. endelse
  553. end
  554.  
  555.  
  556.  
  557. PRO draw_cube, c0, c1, faces, color
  558. ;    draw a cube whose opposite corners are [c0[0],c0(1),c0(2)],
  559. ;    and [c1[0], c1(1), p2(3)].
  560. ;    color = drawing color.
  561. COMMON volume_data, a
  562. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  563. p0 = intarr(3,8)
  564. p1 = float(p0)
  565. cc = [[c0],[c1]]
  566. for i=0,7 do BEGIN
  567.     p0[0,i] = [ cc[0, i and 1], cc[1, (i/2 and 1)], cc[2, (i/4 and 1)]]
  568.     p1[0,i] = convert_coord(p0[*,i], /T3D,/TO_DEVICE,/DATA)
  569.     ENDFOR
  570.  
  571. if n_elements(color) le 0 THEN color = sl.nc1
  572. f = sl.facevs
  573. flags = bytarr(8,8)    ;line flags, dont draw same line twice
  574. for i=0,n_elements(faces)-1 do BEGIN
  575.     ff = [ f[*,faces[i]], f[0,faces[i]]]  ;Vertex indices
  576.     for j=0,3 do begin
  577.     k = ff[j] < ff[j+1] & l = ff[j] > ff[j+1]
  578.     if not flags[k,l] then plots, p1[*,[k,l]], color = color, /dev
  579.     flags[k,l] = 1
  580.     ENDFOR
  581.     ENDFOR
  582. end
  583.  
  584.  
  585.  
  586.  
  587.  
  588. PRO slicer_erase        ;draw the background
  589. ;    call with no params to erase all.
  590. COMMON volume_data, a
  591. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  592.  
  593. SLICER_JOURNAL, "ERASE"
  594. set_plot,'Z'
  595. erase
  596. sl.p1 = convert_coord(sl.p0, /T3D, /TO_DEVICE, /DATA)  ;save dev coords
  597. s = strarr(8)
  598. for i=0,7 do BEGIN
  599.     s[i] = string(sl.p0[*,i],format ="(' (',i0,',',i0,',',i0,')')")
  600.     ENDFOR
  601. junk = max(sl.p1[2,*], j)
  602. sl.v_close = j            ;index of closest vertex
  603. p = where(sl.facevs eq sl.v_close)/4   ;indices of closest verts
  604. colors = [ sl.nc1, sl.nc3*3+1]  ;white, green
  605. for i=0,5 do BEGIN        ;draw faces
  606.     k= (where(p eq i))[0] lt 0     ;1 = not close, 0 = close
  607.     draw_cube, [0,0,0], dims-1, i, colors[k]
  608.     ENDFOR
  609. for i=0,7 do xyouts, sl.p1[0,i],sl.p1[1,i],/DEVICE,s[i], $
  610.     color=colors[i ne sl.v_close]
  611. z_last = tvrd()
  612. zb_last = tvrd(CHANNEL=1, /WORDS)
  613. slicer_show
  614. end
  615.  
  616.  
  617.  
  618. Function slicer_plane_int, dummy
  619. ; Return the intersections of the plane with the volume cube.
  620. ; V[3,12] = intersections of plane with the 12 edges.
  621. ; Flags[12] = 1 if there is an intersection at that edge.
  622. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  623.  
  624. Jn = sl.orthop[0:2]            ;Plane eqn
  625. Jd = sl.orthop[3]
  626.  
  627. v = fltarr(3,12)
  628. k = 0
  629.  
  630. for i=0,11 do begin            ;Faces
  631.     p0 = sl.p0[*,sl.edges[0,i]]        ;Beginning of edge
  632.     p1 = sl.p0[*,sl.edges[1,i]]        ;End of edge
  633.     lv = p1-p0
  634.     t = total(lv * Jn)
  635.     if t ne 0 then begin
  636.     t = -(jd + total(p0 * Jn)) / t
  637.     p = p0 + t * lv            ;Point of intersection
  638.     d = min((p - p0) * (p1-p))
  639.     if d ge 0.0 then begin        ;Within edge?
  640.         v[0,k] = p            ;Yes, save intersection
  641.         k = k + 1
  642.         endif          
  643.     endif                ;T ne 0
  644.     endfor                    ;i
  645.  
  646. ; Sort into order:
  647. d = max(abs(Jn), m)            ;Largest plane coeff = what we ignore
  648. u = v[[m+1, m+2] mod 3, 0:k-1]        ;Get other 2 coords
  649. a = fltarr(k)                ;Angle measure
  650. d = min(u[1,*], dmin)            ;Get lowest point
  651. ;p0 = u[*,dmi])
  652. ;for i=0,k-1 do if i ne dmin then begin    ;Get angles
  653. ;    d = u[*,i] - p0            ;Dx,dy
  654. ;    d0 = total(abs(d))        ;abs(dx) + abs(dy)
  655. ;    if d0 ne 0. then begin
  656. ;        t = d(1) / d0        ;Proportional to angle w. horizontal
  657. ;        if d[0] lt 0. then t = 2. - t $
  658. ;        else if d(1) lt 0. then t = t + 4
  659. ;        endif else t = 0.
  660. ;    a[i] = t
  661. ;    endif
  662. u_dx = u[0,*]-u[0,dmin]
  663. u_dy = u[1,*]-u[1,dmin]
  664. zero_ind = Where((u_dx EQ 0.0) AND (u_dy EQ 0.0))
  665. if (zero_ind[0] GE 0L) THEN u_dx[zero_ind] = 1.0
  666. a=atan(u_dy, u_dx)
  667. zero_ind=0 & u_dx=0 & u_dy=0
  668. a[dmin] = -100.                ;Anchor = first
  669. n = sort(a)                ;Go around anchor point & back
  670. return, v[*, [n, n[0]]]
  671. end
  672.  
  673. PRO slicer_show, image
  674. ;move the Z buffer to the X display.  leave device set to X.
  675. ; if parameter is present, show it rather than reading the Z buffer
  676. COMMON volume_data, a
  677. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  678.  
  679. if n_params() eq 0 then begin
  680.     set_plot,'Z'
  681.     image = tvrd()
  682.     endif
  683. set_plot,sl.gdev
  684. wset, sl.window
  685. tv, image
  686. sl.cube_on = 0
  687. end
  688.  
  689. PRO draw_orientation    ;draw the orientation cube in the small window
  690. ; Draw the outline of the 3 frontmost faces of the main cube.
  691. ; Draw the fixed axis plane in green.
  692. ; If the mode is cut or cube, draw the selected cube.  Draw the back faces
  693. ;    in blue, and label the selection points.
  694.  
  695. COMMON volume_data, a
  696. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  697. COMMON slicer_common1, old_slice, d0, z0, az, el
  698.  
  699. i = sl.mode_bases[mode]
  700. widget_control, i, get_uvalue = draw        ;the widget id
  701. widget_control, draw[0], get_value=window    ;the window number
  702. wset, window
  703. device, set_graph = 3                ;Copy mode
  704. kc = 3 * sl.nc3 + 1                ;Drawing color
  705. erase
  706.  
  707. if mode le 0 then begin            ;Single slice?
  708.     if sl.ortho eq 0 then begin        ;Orthogonal?
  709.     mark_oblique, kc
  710.     goto, done
  711.     endif
  712.     z = [0,0,0]
  713.     d1 = dims-1
  714.   endif else begin            ;Block.
  715.     z = sl.p0cube[*,0] < sl.p0cube[*,1]
  716.     d1 = sl.p0cube[*,0] > sl.p0cube[*,1]
  717.   endelse
  718.                     ; draw fixed plane:
  719. nlines = 6
  720. p = z
  721. d = (d1-z) / float(nlines-1)
  722.  
  723. p[fixed] = (d1[fixed] + z[fixed])/2.
  724. d[fixed] = 0.0
  725.  
  726. for i=0,nlines-1 do BEGIN        ;draw fixed direction
  727.     xx = replicate(p[0],2)
  728.     yy = replicate(p[1],2)
  729.     zz = replicate(p[2],2)
  730.     if fixed ne 0 THEN plots, [z[0],d1[0]], yy,zz, /T3D, COLOR=kc, /DATA
  731.     if fixed ne 1 THEN plots, xx, [z[1],d1[1]],zz, /T3D, COLOR=kc, /DATA
  732.     if fixed ne 2 THEN plots, xx, yy, [z[2],d1[2]],/T3D, COLOR=kc, /DATA
  733.     p = p + d
  734.     ENDFOR
  735.  
  736. if mode ne 0 then begin        ;Do cube
  737.     draw_cube, sl.p0cube[*,0], sl.p0cube[*,1], indgen(6), kc+1  ;all faces
  738.         ;Close faces in white
  739.     draw_cube, sl.p0cube[*,0], sl.p0cube[*,1], $
  740.             where(sl.facevs eq sl.v_close)/4
  741.     for i=0,1 do begin        ;Label them
  742.         p = convert_coord(sl.p0cube[*,i], /T3D, /TO_DEV, /DATA)
  743.         xyouts, p[0], p[1], strtrim(i,2), /device
  744.         endfor
  745.     endif
  746.  
  747. done: 
  748. draw_cube, [0,0,0], dims-1, where(sl.facevs eq sl.v_close)/4  ;draw close faces
  749. wset, sl.window
  750. return
  751. end
  752.  
  753.  
  754. PRO mark_oblique, color            ;Draw an oblique slice
  755. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  756. COMMON slicer_common1, old_slice, d0, z0, az, el
  757.  
  758. if n_elements(d0) lt 3 then return
  759.  
  760. plots, d0, /T3D, COLOR=color, /DATA
  761. z1 = [[z0], [z0]]
  762. for i=0,2 do begin
  763.     z2 = z1
  764.     z2[i,0] = 0. & z2[i,1] = dims[i]-1.
  765.     plots, z2, /T3D, COLOR = color, /DATA
  766.     endfor
  767. return
  768. end
  769.  
  770.  
  771.  
  772. PRO mark_slice, ev        ;mark a horizontal or vertical slice
  773.  
  774. COMMON volume_data, a
  775. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  776. COMMON slicer_common1, old_slice, d0, z0, az, el
  777.  
  778. ;        loop until the mouse is released.
  779. oldbuttons = sl.lbuttons
  780. sl.lbuttons = oldbuttons and (not ev.release) or (ev.press)
  781. press = ev.press and 1            ;New left button press?
  782. p = float([ev.x, ev.y])            ;device coords of mouse
  783.  
  784. if (n_elements(old_slice) le 0) or (ev.press ne 0) then old_slice = -1
  785. kslice = -1                ;assume no face
  786. kc = sl.xcol                ;XOR drawing color
  787.  
  788. if sl.lbuttons and 1 THEN BEGIN        ;Marking a face?
  789.     f = where(sl.facevs eq sl.v_close)/4  ;3 faces to check that are front
  790.     d1 = dims-1
  791.     z1 = intarr(3)
  792.     d = ''
  793.     for i=0,2 do BEGIN            ;find the face
  794.     j = f[i]            ;face index
  795.     p1 = sl.p1[0:1, sl.facevs[*,j]]    ;vertices
  796.     if p_inside_poly(p1, p) THEN BEGIN
  797.         face = j
  798.         p = p / [ !d.x_size, !d.y_size]    ;Get data coords. normalized
  799.         face_dim = face mod 3    ;Fixed coord along face
  800.         if face le 2 THEN k = 0 ELSE k = dims[face_dim]-1
  801.         p = COORD2to3(p[0], p[1], face_dim, k, sl.pt_inverse)
  802.         ip = fix(p + 0.5)        ;round
  803.         if ip[fixed] ge dims[fixed] then goto, NO_BREAK    ;Outside
  804.         kslice = ip[fixed]        ;slice number
  805.         d1[fixed] = kslice
  806.         z1[fixed] = kslice
  807.         goto, NO_BREAK
  808.         ENDIF
  809.     ENDFOR
  810.   NO_BREAK:
  811. ENDIF                    ;Marking a face
  812.  
  813. device, SET_GRAPH=6             ;set XOR mode
  814. valid = kslice ge 0
  815.  
  816. if sl.ortho eq 0 then begin        ;Oblique???
  817.     if n_elements(az) eq 0 then begin    ;Initialize?
  818.     az = 0.  & el = 0. & z0 = dims / 2.
  819.     sl.orthop = [ 0., 0., 1., -total(dims)/2]
  820.     endif
  821.     el1 = el & az1 = az & z1 = z0    ;Old params
  822.     if (sl.lbuttons and 4) ne 0 then begin    ;New azimuth/elev?
  823.     if sl.oangle then $
  824.         el1 = fix((p[0]/!d.x_size * 198) - 99.) > (-90) < 90 $
  825.     else az1 = fix((p[0]/!d.x_size * 396) - 198.) > (-180) < 180
  826.     if (el1 ne el) or (az1 ne az) then begin
  827.         s = sin(el1 * !dtor)
  828.         sl.orthop[0] = sin(-az1 * !dtor) * s
  829.         sl.orthop[1] = cos(-az1 * !dtor) * s
  830.         sl.orthop[2] = cos(el1 * !dtor)
  831.         valid = 1
  832.         endif
  833.     endif else if valid then begin    ;New origin?
  834.     p[face_dim] = z0[face_dim]    ;New coords, 1 remains unchanged
  835.     z1 = p
  836.     valid = total(abs(z0-z1)) ne 0.    ;Change...
  837.     ENDIF
  838.  
  839.     if (valid) then begin        ;Draw new
  840.     sl.orthop[3] = -total(sl.orthop * z0)
  841.         IF old_slice gt 0 THEN mark_oblique, kc    ;Erase old
  842.     old_slice = 0
  843.     el = el1 & az = az1 & z0 = z1    ;New parameters
  844.     if valid and (sl.lbuttons ne 0) THEN BEGIN  ;Update obliq outline
  845.         WIDGET_CONTROL, sl.pos_text, set_value = $
  846.         STRING(z0, az, el, FORMAT="('(',3f5.1,') A=', i4, ' E=',i4)")
  847.         d0 = slicer_plane_int()        ;New intersections
  848.         mark_oblique, kc    ;Draw new
  849.         old_slice = 1        ;show its visible
  850.         ENDIF
  851.     ENDIF            ;Valid
  852.     if ev.release ne 0 then begin    ;Released button?
  853.     if old_slice then mark_oblique, kc
  854.     draw_orientation    ;Draw resulting plane
  855.     old_slice = 0
  856.     endif
  857. ENDIF ELSE BEGIN            ;Orthogonal.
  858.     IF (kslice ne old_slice) THEN BEGIN ;Movement?
  859.         if (press eq 0) and (old_slice ge 0)then $    ;Erase old?
  860.         draw_cube, z0, d0, fixed, kc
  861.     if valid then $
  862.           d = 'Position: ' + string(ip, format="('(',i4,',',i4,',',i4,')')") $
  863.     else d = ''
  864.     WIDGET_CONTROL, sl.pos_text, set_value=d
  865.     if valid and sl.lbuttons THEN BEGIN
  866.         draw_cube, z1, d1, fixed, kc
  867.         z0 = z1
  868.         d0 = d1
  869.         ENDIF
  870.     IF (ev.release eq 1) and (old_slice ge 0) THEN BEGIN
  871.         device, SET_GRAPH=3
  872.         slicer_draw, fixed, old_slice    ;Mark the slice
  873.         ENDIF            ;Release
  874.     old_slice = kslice        ;Save current position
  875.     ENDIF                ;Movement
  876. ENDELSE
  877.  
  878. device, SET_GRAPH=3    ;normal mode
  879. end
  880.  
  881.  
  882. PRO do_cube                ;Draw a cube or cut
  883. COMMON volume_data, a
  884. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  885.  
  886. WIDGET_CONTROL, sl.base, /HOURGLASS
  887. SET_PLOT, 'Z'
  888. z =  (z_last = tvrd())            ;Save previous image & current cont
  889. zb = (zb_last = tvrd(CHANNEL=1, /WORDS))
  890.  
  891.  
  892. SLICER_JOURNAL, "TRANS", [sl.trans, sl.threshold * 100. / sl.nc3]
  893. SLICER_JOURNAL, "CUBE", [ mode, sl.cut_ovr, sl.interp, reform(sl.p0cube, 6) ]
  894.  
  895. d0 = sl.p0cube[*,0] < sl.p0cube[*,1]        ;Lower corner
  896. d1 =  (sl.p0cube[*,0] > sl.p0cube[*,1]) -d0
  897. coords = fltarr(3,8)
  898. for i=0,7 do coords[0,i] = $        ;Verts of our cube
  899.    [ (i and 1) * d1[0], (i and 2)/2 *d1[1], (i and 4)/4 * d1[2]] + d0
  900. faces = where(sl.facevs eq sl.v_close)/4   ;close faces
  901. relation = mode eq 1
  902.  
  903. FOR face = 0, 5 do $            ;Draw the faces of the cube or cut
  904.   IF ((where(face eq faces))[0] ge 0) eq relation then begin  ;Do this face?
  905.     v = 0 & ones = 0 & z0 = 0 & q = 0    ;Clear things out
  906.     erase                    ;Reset Z buffer
  907.     verts = sl.facevs[*,face]        ;Vertices
  908.     polyfill, coords[*, verts], /T3D    ;Draw polygon for face
  909.     z0 = tvrd(CHANNEL=1, /WORDS)        ;Now read the Z buffer
  910.     if mode eq 1 then $            ;Cube? or Cut?
  911.         points = where(z0 gt zb) $    ;New points for cube
  912.     else if sl.cut_ovr then points = where(z0 ne z0[0,0]) $ ;Cut mode?
  913.     else points = where((z0 ne z0[0,0] and (zb gt z0)))  ;Over mode
  914.  
  915.     widget_control, sl.pos_text, set_value = $
  916.         'Creating face ' + strtrim(face,2)
  917.     if points[0] ne -1 THEN    BEGIN        ;Anything to do?
  918. ;        Get volume coords of plane:
  919.       v = p_inverse(points mod !d.x_size, points / !d.x_size, z0[points])
  920. ;        Either interpolate or pick nearest neighbor
  921.       widget_control, sl.pos_text, set_value = $
  922.         (['Sampling','Interpolating'])[sl.interp] + $
  923.         ' face ' + strtrim(face,2) + ',  ' + $
  924.         strtrim(n_elements(v)/3,2) + ' Pixels'
  925.  
  926.       if sl.interp THEN v = interpolate(a, v[*,0], v[*,1], v[*,2]) $
  927.       else begin
  928.         v = round(v)
  929.         v = a[long(temporary(v)) # [1, dims[0], dims[0] * dims[1]]]
  930.         endelse
  931.                     ;Update our points
  932.       if sl.trans THEN BEGIN    ;Transparency?
  933.         good = where(v ge sl.threshold, count)
  934.         if count le 0 then goto, skipit
  935.         v = v[good]
  936.         points = points[good]
  937.         endif
  938.       offset = byte((face mod 3) * sl.nc3)   ;Offset
  939.       q = bytscl(v, max=sl.amax, min=sl.amin, top = sl.nc3-1) ;face data
  940.                    ;Get subscripts in data cube
  941.       if offset ne 0 then q = q + offset
  942.       z[points] = q            ;Store the new face
  943.       zb[points] = z0[points]    ;in both buffers
  944.     skipit:
  945.     ENDIF                ;Anything to do
  946.   ENDIF                    ;Each face
  947. tv, z                    ;Now show it
  948. tv, zb, /WORDS, CHANNEL=1        ;and update depth buffer
  949. v = 0 & ones = 0 & z0 = 0 & q = 0    ;Clear things out
  950. z = 0 & zb = 0
  951. widget_control, sl.pos_text, set_value = 'Done.'
  952. slicer_show
  953. end
  954.  
  955.  
  956.  
  957.  
  958. PRO mark_cube1, p0, ip    ;Draw the outline of the cube in the main drawable
  959. ; p0 = cube coordinates (3,2).
  960. ; ip = index of corner that is marked (0 or 1).
  961. COMMON volume_data, a
  962. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  963.  
  964. draw_cube, p0[*,0],p0[*,1], indgen(6), sl.xcol   ;Basic cube
  965. p1 = [[p0[*,ip]], [p0[*,ip]]]
  966. p = sl.p0[*,sl.v_close]
  967. for i=0,2 do begin        ;Lines to faces
  968.     p1[i,0] = p[i]
  969.     plots, p1, color=128, /T3D
  970.     p1[i,0] = p1[i,1]
  971.     endfor
  972. end
  973.  
  974.  
  975.  
  976. PRO mark_cube, ev            ;Mark a cube in the main window
  977. ;  Use the XOR graphics mode to avoid killing the display
  978. COMMON volume_data, a
  979. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  980.  
  981. if n_params() eq 0 then    begin        ;Erase old cube?
  982.     device, SET_GRAPHICS = 6    ;Set XOR mode
  983.     if sl.cube_on then mark_cube1, sl.p0cube, sl.cube_ip
  984.     sl.cube_on = 0
  985.     device, SET_GRAPHICS=3
  986.     return
  987.     ENDIF
  988.  
  989. oldbuttons = sl.lbuttons
  990. sl.lbuttons = oldbuttons and (not ev.release) or (ev.press)
  991. press = ev.press and 1            ;New left button press?
  992.  
  993. if sl.lbuttons eq 0 then begin        ;Released all buttons?
  994.     if oldbuttons ne 0 then draw_orientation  ;Update viewbox
  995.     return
  996.     ENDIF
  997.  
  998. x = ev.x / float(!d.x_size)        ;Normalized coords
  999. y = ev.y / float(!d.y_size)
  1000. d1 = dims -1
  1001.  
  1002. p0cube = sl.p0cube        ;Save old coords
  1003. cube_ip = sl.cube_ip
  1004.  
  1005. sl.cube_ip = sl.lbuttons eq 2        ;Corner index
  1006. q = sl.p0cube[fixed, sl.cube_ip]    ;Fixed axis/point
  1007. p = fix(COORD2TO3(x, y, fixed, q, pti)+0.5) ;3D coords
  1008. sl.p0cube[*,sl.cube_ip] = p < d1 > 0    ;New corner value
  1009. sl.p0cube[fixed, sl.cube_ip] = q
  1010. if (total(abs(sl.p0cube - p0cube)) eq 0.0) and $ ;No change?
  1011.    cube_ip eq sl.cube_ip then return
  1012.  
  1013. device, SET_GRAPHICS = 6    ;Set XOR mode
  1014. if sl.cube_on then mark_cube1, p0cube, cube_ip  ;Erase prev
  1015. sl.cube_on = 1
  1016. mark_cube1, sl.p0cube, sl.cube_ip
  1017. d = string(sl.p0cube, format="('(', 3i4, ') (', 3i4, ')')")
  1018. widget_control, sl.pos_text, set_value = d  ;label it
  1019. DEVICE, SET_GRAPHICS = 3        ;Restore
  1020. end
  1021.  
  1022.  
  1023.  
  1024.  
  1025.  
  1026. PRO slicer_event, ev
  1027. COMMON volume_data, a
  1028. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  1029.  
  1030.  
  1031. swin = !d.window
  1032. wset, sl.window        ;Our window
  1033.  
  1034. if ev.id eq sl.draw THEN BEGIN        ;mouse press?
  1035.   IF mode le 2 THEN BEGIN        ;Slice or cube mode?
  1036.     IF  ((ev.press and 4) ne 0) and sl.ortho THEN BEGIN  ;Right but= chg plane?
  1037.     fixed = (fixed + 1) mod 3    ;bump plane
  1038.     draw_orientation
  1039.     goto, clean_exit
  1040.     ENDIF    
  1041.     if mode eq 0 then BEGIN        ;Slice mode?
  1042.     if (ev.press and 2) ne 0 then goto, probe_it  ;Middle = probe
  1043.     i = sl.lbuttons or ev.press    ;New state
  1044.     if ((sl.ortho eq 0) and (i ne 0)) or (sl.ortho and i) THEN BEGIN
  1045.         mark_slice, ev        ;mark the slice
  1046.         goto, clean_exit
  1047.         endif
  1048.     ENDIF ELSE if mode le 2 THEN BEGIN
  1049.     mark_cube, ev             ;Move the cube
  1050.     ENDIF
  1051.     goto, clean_exit
  1052.   ENDIF    ELSE BEGIN            ;Other modes
  1053.     if ev.press eq 0 then goto, clean_exit
  1054.   probe_it: if (n_elements(zb_last) le 1) THEN goto, clean_exit
  1055.     set_plot,'Z'
  1056.     z = tvrd(ev.x, ev.y, /WORD, /CHANNEL)  ;Z-buffer value at x,y
  1057.     set_plot,sl.gdev
  1058.     d = 'No Data Value'
  1059.     if z[0] gt -32760 THEN BEGIN    ;anything there?
  1060.       p = p_inverse(ev.x, ev.y, z[0])  ;To object coords
  1061.       p = round(p)            ;round
  1062.       p = p > 0 < (dims-1)        ;to range
  1063.       x = a[p[0], p[1], p[2]] + 0
  1064.       y = fix(100.*(x - sl.amin)/(sl.amax - sl.amin))  ;To %
  1065.       d = 'Position: '+string(p,format="('(',i0,',',i0,',',i0,')')") + $
  1066.         ', Data= ' + strtrim(x,2) + ' (' + strtrim(y,2) + '%)'
  1067.     ENDIF            ;Something there
  1068.     widget_control, sl.pos_text, set_value = d
  1069.   ENDELSE
  1070.   goto, clean_exit
  1071. ENDIF            ;Drawable window
  1072.  
  1073. if ev.id eq sl.isop.drawable then begin        ;Isosurface threshold
  1074.     if ev.press eq 0 then goto, clean_exit
  1075.     x = (ev.x - sl.isop.xs[0]) / sl.isop.xs[1]
  1076.     x = x > sl.amin < sl.amax
  1077.     WIDGET_CONTROL, sl.isop.slider, $
  1078.        SET_VALUE = 100.*(x - sl.amin) / (sl.amax-sl.amin)
  1079.     sl.isop.value = x
  1080.     goto, clean_exit
  1081.     ENDIF
  1082. if ev.id eq sl.file_text[0] then $
  1083.     goto, clean_exit             ;Ignore return in file name widget
  1084. if ev.id eq sl.rslide[2] then BEGIN
  1085.     slicer_orientation
  1086.     goto, clean_exit
  1087.     ENDIF
  1088. ;        here, it must be a button or a slider:
  1089. widget_control, ev.id, get_uvalue = eventval
  1090. case eventval of
  1091. "CANCUBE" : mark_cube        ;Undraw outline
  1092. "COLORS" : slicer_colors, (where(sl.color_button eq ev.id))[0]
  1093. "CUTINTO": sl.cut_ovr = 0
  1094. "CUTOVER": sl.cut_ovr = 1
  1095. "ERASE"  : slicer_erase
  1096. "EXIT"   : BEGIN
  1097.     widget_control, ev.top, /DESTROY
  1098.     if sl.rbase ne 0 then WIDGET_CONTROL, sl.rbase, /DESTROY
  1099.     z_last = 0
  1100.     zb_last = 0
  1101.     goto, close_journal
  1102.     ENDCASE
  1103. "EXPOSE0": sl.expose = 0
  1104. "EXPOSE1": sl.expose = 1
  1105. "GOCUBE" : do_cube
  1106. "HELP" : BEGIN
  1107.     xdisplayfile, filepath("slicer.txt", subdir=['help', 'widget']), $
  1108.         title = "Slicer help", $
  1109.         group = ev.top, $
  1110.         width = 72, height = 24
  1111.     goto, clean_exit
  1112.     ENDCASE
  1113.  
  1114. "INTERP0": BEGIN
  1115.     sl.interp = 0
  1116.     goto, set_interp
  1117.     ENDCASE
  1118. "INTERP1": BEGIN
  1119.     sl.interp = 1
  1120.   set_interp:  i = WIDGET_INFO(ev.id, /parent)
  1121.     WIDGET_CONTROL, i, GET_UVALUE = i    ;Buttons
  1122.     WIDGET_CONTROL, i[1-sl.interp], /SENS
  1123.     WIDGET_CONTROL, i[sl.interp], SENS=0
  1124.     ENDCASE
  1125.  
  1126. "ORTHO0":  BEGIN            ;On oblique
  1127.     sl.ortho = 0
  1128.     WIDGET_CONTROL, sl.obuttons, MAP=1
  1129.     draw_orientation
  1130.     ENDCASE
  1131. "ORTHO1":  BEGIN
  1132.     sl.ortho = 1
  1133.     WIDGET_CONTROL, sl.obuttons, MAP=0
  1134.     draw_orientation
  1135.     ENDCASE
  1136. "AZIM" : sl.oangle = 0
  1137. "ELEV" : sl.oangle = 1
  1138. "GOOBL" :  BEGIN            ;Do an oblique slice
  1139.     WIDGET_CONTROL, ev.top, /HOURGLASS
  1140.     slicer_oblique
  1141.     end
  1142.  
  1143.  
  1144. "ORIENTATION": SLICER_ORIENTATION, (where(sl.ori_butt eq ev.id))[0]
  1145. "PLAYBACK" : BEGIN
  1146.     WIDGET_CONTROL, sl.file_text[0], GET_VALUE=name
  1147.     name = strtrim(name[0],2)
  1148.     SLICER_PLAYBACK, FILE = name
  1149.     ENDCASE
  1150. "RECORD" : BEGIN
  1151. start_journal: if sl.journal ne 0 then free_lun, sl.journal  ;Close old
  1152.     sl.journal = 0
  1153.     WIDGET_CONTROL, sl.file_text[0], GET_VALUE=name
  1154.     name = strtrim(name[0])
  1155.     openw, i, name, ERROR=j, /GET_LUN
  1156.     if j ne 0 then begin        ;OK?
  1157.         widget_control, sl.file_text[1], set_value = !ERR_STRING
  1158.         goto, clean_exit
  1159.         ENDIF
  1160.     widget_control, sl.file_text[1], set_value = 'Journal Active'
  1161.     sl.journal = i
  1162.     ENDCASE
  1163. "RECORDOFF" : BEGIN
  1164.     widget_control, sl.file_text[1], set_value = 'Journal Closed'
  1165. close_journal: if sl.journal ne 0 then free_lun, sl.journal  ;Close old
  1166.     sl.journal = 0
  1167.     ENDCASE
  1168. "THRESHOLD" : BEGIN
  1169.     sl.threshold = sl.nc3 * ev.value / 100.
  1170.     sl.trans = (ev.value ge 1) and (ev.value le 99)  ;On if reasonable
  1171.     ENDCASE
  1172. "HIGH": sl.isop.hi_lo = 0
  1173. "LOW" : sl.isop.hi_lo = 1
  1174. "ISOSLIDE" : sl.isop.value = (ev.value / 100.)*(sl.amax-sl.amin) + sl.amin
  1175. "GO":   do_isosurface
  1176. "SHADING": BEGIN
  1177.     sl.shading = ev.value /100.
  1178.     slicer_colors
  1179.     ENDCASE
  1180. "STMAX": BEGIN
  1181.     sl.stretch[1] = ev.value
  1182.     slicer_colors
  1183.     ENDCASE
  1184. "STMIN": BEGIN
  1185.     sl.stretch[0] = ev.value
  1186.     slicer_colors
  1187.     ENDCASE
  1188. "UNDO" : slicer_undo
  1189. "XROTATION": BEGIN
  1190.     sl.rotation[0] = ev.value
  1191.     slicer_orientation
  1192.     ENDCASE
  1193. "ZROTATION": BEGIN
  1194.     sl.rotation[1] = ev.value
  1195.     slicer_orientation
  1196.     ENDCASE
  1197.  
  1198. ELSE :   BEGIN            ;mode button?
  1199.     k = where(eventval eq sl.mode_names, count)  ;Match with mode name?
  1200.     if count eq 1 THEN BEGIN        ;switch mode
  1201.         if sl.cube_on then mark_cube    ;Remove the cube if vis
  1202.         fixed = 0            ;Reset fixed direction
  1203.         if sl.mode_bases[mode] ne 0 THEN $  ;Remove panel if mapped
  1204.             WIDGET_CONTROL, sl.mode_bases[mode], MAP=0
  1205.         mode = k[0]            ;New mode
  1206.         if sl.mode_bases[mode] ne 0 THEN $  ;Map new base
  1207.             WIDGET_CONTROL, sl.mode_bases[mode], MAP=1
  1208.         if mode le 2 THEN BEGIN        ;Slice or cube?
  1209.             draw_orientation
  1210.             ENDIF
  1211.         if mode eq 3 THEN BEGIN        ;Draw histogram
  1212.             WSET, sl.isop.window
  1213.             type = size(a)
  1214.             int = type[type[0] + 1] le 3  ;True if int type
  1215.             j = (sl.amax -sl.amin)/100. ;bin size
  1216.             if int then j = j > 1
  1217.             h = histogram(a, max=sl.amax, min = sl.amin, bin=j)
  1218.             if int THEN j = fix(j + .99)
  1219.             k = sort(h)
  1220.             n = n_elements(h)
  1221.             x = findgen(n) * j + sl.amin < sl.amax
  1222.             xsave = !x.s & ysave = !y.s
  1223.             PLOT,x,h, xst = 9, yst=8, ymargin=[2,0], $
  1224.                 yrange= [0,h[k[n-8]]], yticks=1, chars=.75, $
  1225.                 xticks=4
  1226.             sl.isop.xs = !x.s * !d.x_size
  1227.             WSET, sl.window
  1228.             !x.s = xsave & !y.s = ysave
  1229.             ENDIF            ;Isosurface
  1230.         widget_control, sl.obuttons, $    ;Oblique controls
  1231.             MAP = (mode eq 0) and (sl.ortho eq 0)
  1232.         goto, clean_exit
  1233.     ENDIF
  1234.     print,'Unknown event: ', eventval
  1235.     help, /STRUCT, ev
  1236.     ENDCASE
  1237. ENDCASE
  1238.  
  1239. clean_exit:
  1240.   wset, swin
  1241. end
  1242.  
  1243. PRO slicer, GROUP = group, RANGE = range, COMMANDS = commands, $
  1244.     CMD_FILE = cmd_file, RESOLUTION = resolution, DETACHED = detached, $
  1245.         MODAL = modal
  1246. ;+
  1247. ; NAME:
  1248. ;    SLICER
  1249. ;
  1250. ; PURPOSE:
  1251. ;    Widget based application to show 3D volume slices and isosurfaces.
  1252. ;
  1253. ; CATEGORY:
  1254. ;    Volume display / rendering.
  1255. ;
  1256. ; CALLING SEQUENCE:
  1257. ;    COMMON VOLUME_DATA, A
  1258. ;    A = your_volume_data
  1259. ;    SLICER
  1260. ;
  1261. ; INPUTS:
  1262. ;    Variable A in VOLUME_DATA common contains volume data.  See EXAMPLE
  1263. ;    section below.
  1264. ;
  1265. ; KEYWORD PARAMETERS:
  1266. ;     COMMANDS:    An optional string array of commands to execute
  1267. ;        before entering the interactive mode.  Commands are
  1268. ;        in the form of a keyword optionally followed one or more 
  1269. ;        numeric, blank-separated parameters.  For example:
  1270. ;            "COMMAND P1 P2 P3 ... Pn"
  1271. ;        Keywords and parameters are:
  1272. ;        UNDO:    Undo previous operation.
  1273. ;        ORI X_Axis Y_Axis Z_axis X_Rev Y_Rev Z_Rev X_Rot Z_Rot Asp
  1274. ;            This command sets the orientation for the SLICER 
  1275. ;            display.  X_Axis, Y_Axis, and Z_Axis should be 0 for 
  1276. ;            data x, 1 for data y, and 2 for data z.  
  1277. ;            X_Rev, Y_Rev, and Z_Rev should be 0 for normal, 1 for 
  1278. ;            reversed.  Asp is the Z axis aspect ratio w/ respect 
  1279. ;            to X, Y.  X_Rot and Z_Rot are the rotations of the 
  1280. ;            X and Z axes in degrees (30 is the default).
  1281. ;            For example, to interchange the X and Z axes and
  1282. ;            reverse the Y use the string:
  1283. ;                ORI 2 1 0 0 1 0 30 30
  1284. ;        TRANS On_Off Threshold:  Use this command to turn transparency 
  1285. ;            on or off and set the transparency threshold value.
  1286. ;            1 means on, 0 means off.  Threshold is expressed in 
  1287. ;            percent of data range (0 = min data value, 100 = max 
  1288. ;            data value).
  1289. ;        SLICE Axis Value Interp 0:  Draw an orthogonal slice along
  1290. ;            the given axis (0=x, 1=y, 2=z) at Value.  Set Interp
  1291. ;            equal to 1 for interpolation, 0 for nearest neighbor.
  1292. ;            Expose = 1 to remove, 0 for normal slice.
  1293. ;        SLICE Azimuth, Elev, Interp, Expose, 1, x0, y0, z0:  Draw
  1294. ;            an oblique slice.  The oblique plane crosses the
  1295. ;            XY plane at angle Azimuth, with an elevation of Elev.
  1296. ;            It passes thru the point (x0, y0, z0).
  1297. ;        COLOR Table_Index Low High Shading:  Set the color tables.
  1298. ;            Table_Index is the pre-defined color table number (see
  1299. ;            LOADCT), or -1 to retain the present table.  Low, High
  1300. ;            and Shading are expressed in percent.
  1301. ;        ISO Threshold Hi_Lo:  Draw an iso-surface.  Threshold is the 
  1302. ;            isosurface threshold value.  Hi_Lo should be set to 1
  1303. ;            to view the low side, 0 for the high side.
  1304. ;        ERASE:    Erase the display.
  1305. ;        CUBE Mode Cut_Ovr Interp X0 Y0 Z0 X1 Y1 Z1:  Draw cube 
  1306. ;            (mode = 1) or cut-out (mode = 0).
  1307. ;            Cut_Ovr should be set to  1 for cut-over, 0 for 
  1308. ;            cut-thru.  Interp should be 1 for interpolation, 0 
  1309. ;            for nearest neighbor.  (X0,Y0,Z0) is the lower corner 
  1310. ;            of the cube.  (X1,Y1,Z1) is the upper corner. 
  1311. ;            (X0 < X1, etc.)
  1312. ;        WAIT Secs:  Wait the designated time (in seconds).
  1313. ;
  1314. ;     CMD_FILE:    A string that contains the name of a file containing SLICER
  1315. ;        commands to execute as described above.
  1316. ;
  1317. ;    DETACHED: if set, put the drawable in a separate window. (Good
  1318. ;        for large windows.)
  1319. ;    GROUP:    The base ID of the widget that calls SLICER.  When this 
  1320. ;        keyword is specified, the death of the caller results in the
  1321. ;        death of the SLICER.
  1322. ;
  1323. ;    RANGE:    A two-element array containing minimum and maximum data
  1324. ;        values of interest.  If this keyword is omitted, the data is 
  1325. ;        scanned for the minimum and maximum.
  1326. ;       MODAL:  If set, then the slicer runs in modal mode.
  1327. ;
  1328. ;    RESOLUTION: a two element vector giving the width and height of
  1329. ;        the drawing window.  Default = 55% by 44% of screen width.
  1330. ; OUTPUTS:
  1331. ;    No explicit outputs.
  1332. ;
  1333. ; COMMON BLOCKS:
  1334. ;    COMMON VOLUME_DATA, A   ;Used to pass in the volume data.
  1335. ;    COMMON SLICER_COMMON   ;Used internally.
  1336. ;    COMMON SLICER_COMMON1  ;Used internally.
  1337. ;
  1338. ; SIDE EFFECTS:
  1339. ;    On exit, the Z-buffer contains the most recent image generated by
  1340. ;    SLICER.  The image may be redisplayed on a different device by 
  1341. ;    reading the Z-buffer contents, plus the current color table.
  1342. ;    Widgets are created on the X window display.
  1343. ;
  1344. ; RESTRICTIONS:
  1345. ;    Widgets are required.
  1346. ;    The volume data must fit in memory.
  1347. ;
  1348. ; PROCEDURE:
  1349. ;    The slicer program has the following modes:
  1350. ;    Slices:         Displays orthogonal slices thru the data volume.
  1351. ;    Block:          Displaces the surfaces of a selected block inside
  1352. ;                    the volume. 
  1353. ;    Cutout:         Cuts blocks from previously drawn objects.
  1354. ;    Isosurface:     Draws an isosurface contour.
  1355. ;    Probe:          Displays the position and value of objects
  1356. ;                    using the mouse.
  1357. ;    Colors:         Manipulates the color tables and contrast.
  1358. ;    Rotations:      Sets the orientation of the display.
  1359. ;
  1360. ; EXAMPLE:
  1361. ;    Data is transferred to the SLICER via the VOLUME_DATA common block
  1362. ;    instead of as an argument.  This technique is used because volume
  1363. ;    datasets can be very large and hence, the duplication that occurs when
  1364. ;    passing values as arguments is a waste of memory.  Suppose that you 
  1365. ;    want to read some data from the file "head.dat" into IDL for use
  1366. ;    in the SLICER.  Before you read the data, establish the VOLUME_DATA
  1367. ;    common block with the command:
  1368. ;
  1369. ;        COMMON VOLUME_DATA, VOL
  1370. ;
  1371. ;    The VOLUME_DATA common block has just one variable in it.  The variable
  1372. ;    can have any name.  Here, we're using the name "VOL".  Now read the
  1373. ;    data from the file into VOL.  For example:
  1374. ;
  1375. ;        OPENR, 1, "head.dat"
  1376. ;        VOL = FLTARR(20, 30, 42)
  1377. ;        READU, 1, VOL
  1378. ;        CLOSE, 1
  1379. ;
  1380. ;    Now you can run the SLICER widget application by entering:
  1381. ;
  1382. ;        SLICER
  1383. ;
  1384. ;    The data stored in VOL is the data being worked on by the SLICER.
  1385. ;
  1386. ;    To obtain the image in the slicer window after slicer is finished:
  1387. ;    (Use the image with the current color tables).
  1388. ;
  1389. ;    SET_PLOT, 'Z'   ;Use the Z buffer graphics device
  1390. ;    a = TVRD()    ;Read the image
  1391. ;
  1392. ; MODIFICATION HISTORY:
  1393. ;    DMS - RSI, Oct, 1991.
  1394. ;    DMS - RSI, Mar, 1992.  Added Journaling and expose mode.
  1395. ;                Fixed bug with 24 bit color.
  1396. ;    DMS - RSI, Jan, 1993.  Added oblique slices.
  1397. ;    bmh - 10/14/93 - The following minor bug fixes.
  1398. ;                  When no elements are found during an iso-surface display,
  1399. ;                  an error message was displayed to an invalid device name.
  1400. ;                  When no oblique slices are selected, the slicer_oblique
  1401. ;                  should return.
  1402. ;       DJC - RSI, Jun, 1994.  Fixed oblique slice initialization and
  1403. ;                              atan(0,0) problem (on HP).
  1404. ;       DJC - RSI, Feb, 1995.  Added modal keyword.
  1405. ;       DJC - RSI, Feb, 1995.  Changed "poly" variable to "polyv" to
  1406. ;                              avoid clash with math "poly" function.
  1407. ;       DJC - RSI, Mar, 1995.  Fixed shading values for iso-surface.
  1408. ;-
  1409.  
  1410.  
  1411.  
  1412. COMMON volume_data, a
  1413. COMMON slicer_common, dims, sl, z_last, zb_last, mode, fixed
  1414. COMMON slicer_common1, old_slice, d0, z0, az, el
  1415.  
  1416.  
  1417.  
  1418. swin = !d.window
  1419. mode = 0
  1420. fixed = 0
  1421. sl_width = 240        ;Slider width
  1422.  
  1423. mode_names = [ 'Slices', 'Block', 'Cutout', 'Isosurface', 'Probe', 'Colors', $
  1424.     'Rotations', 'Journal' ]
  1425. nmodes = n_elements(mode_names)        ;# of modes
  1426.  
  1427. isop = { ISOP, hi_lo : 1, value: 0.0, window : 0, drawable : 0L, slider : 0L, $
  1428.         xs : fltarr(2) }
  1429.  
  1430. ;    Main data structure
  1431. sl = {  SLICER, base : 0L, $        ;Main base
  1432.     draw:0L, $            ;Big drawable
  1433.     window:0, $            ;Big drawable window index
  1434.     trans:0, $            ;Transparency flag
  1435.     threshold_slider: 0L, $        ;Threshold slider 
  1436.     threshold:0b, $            ;Transp threshold in pixel values
  1437.     mode_names : mode_names, $    ;Names of modes
  1438.     interp: 1, $            ;Interpolation flag
  1439.     ortho : 1, $            ;TRUE for orthogonal slices
  1440.     orthop : fltarr(4), $        ;Plane eqn for ortho slices
  1441.     mode_bases : lonarr(nmodes), $    ;Mode panel bases
  1442.     nc3: 0, $            ;# of colors per partition (3 of them)
  1443.     nc1: 0, $            ;# of colors we use
  1444.     amax : 0.0, $            ;Data max, min
  1445.     amin : 0.0, $
  1446.     xcol : 0, $            ;XOR Drawing color
  1447.     color_button:lonarr(24), $    ;Color  table buttons (up to 24)
  1448.     axex: intarr(3), $        ;TRUE to reverse axis
  1449.     axrev: intarr(3), $        ;Axis permutations
  1450.     ori_butt: lonarr(7), $        ;Orientation buttons
  1451.     draw_butt: lonarr(4), $        ;Slice draw/expose buttons
  1452.     pos_text : 0L, $        ;Label widget at bottom
  1453.     rotation: [ 30., 30.], $    ;Current rotations
  1454.     v_close: 0, $            ;Index of closest vertex
  1455.     p0 : fltarr(3,8), $        ;Data coords of cube corners
  1456.     p1 : fltarr(3,8), $        ;Device coords of cube corners
  1457.     pt_inverse : fltarr(4,4), $    ;Inverse of !P.T
  1458.     vfaces : intarr(3,8), $        ;Face index vs vertex index
  1459.     facevs : intarr(4,6), $        ;Vertex index vs faces
  1460.     edges : intarr(2,12), $        ;Vertices vs edge index
  1461.     isop: isop, $            ;Isosurface parameters
  1462.     p0cube : intarr(3,2), $        ;Corner coords of cube selection
  1463.     cut_ovr : 0, $            ;Cut mode
  1464.     cube_on : 0, $            ;If cube is on
  1465.     cube_ip : 0, $            ;Corner of cube
  1466.     shading : 0.20, $        ;Amount of differential shading
  1467.     file_text : LONARR(2), $    ;File name text widgets
  1468.     cslide : LONARR(3), $        ;Color sliders
  1469.     rslide : LONARR(3), $        ;Rotation sliders, aspect text
  1470.     journal : 0, $            ;Journal file
  1471.     stretch : [0,100], $        ;Stretch params
  1472.     lbuttons : 0, $            ;Last button state
  1473.     expose : 0, $            ;Sice mode (0=slice, 1=expose)
  1474.     gdev : !D.NAME, $        ;Graphics device
  1475.     obuttons : 0L, $        ;Oblique buttons
  1476.     oangle : 1, $            ;active angle for oblique
  1477.     rbase: 0L }            ;Drawable base
  1478.  
  1479. ;  Faces vs vertex index
  1480. sl.vfaces = [[0,1,2],[1,2,3],[0,2,4],[2,3,4],[0,1,5], [1,3,5], [0,4,5], $
  1481.         [3,4,5]]
  1482. ;  Vertex indices vs faces  (clockwise order).
  1483. sl.facevs = [ [0,2,6,4], [0,4,5,1], [2,0,1,3], [1,5,7,3], [3,7,6,2], $
  1484.         [6,7,5,4]]
  1485. ;
  1486. ; vertex numbers vs Edge index (12 edges)
  1487. sl.edges = [[0,1],[1,3],[2,3],[0,2], [0,4], [1,5],[2,6],[3,7], $
  1488.       [4,5],[5,7],[6,7],[4,6]]
  1489.  
  1490. if XRegistered("slicer") THEN RETURN
  1491. if n_elements(resolution) lt 2 then begin
  1492.     device, get_screen = resolution
  1493.     resolution[0] = 5 * resolution[0] / 9
  1494.     resolution[1] = 4 * resolution[0] / 5
  1495.     endif
  1496.  
  1497. set_plot,'Z'
  1498. device, /z_buffering, set_resolution = resolution
  1499. set_plot,sl.gdev
  1500.  
  1501. z_last = 0
  1502. zb_last = 0
  1503.  
  1504. s = size(a)
  1505. if s[0] ne 3 THEN $
  1506.     MESSAGE,'Slicer: volume_data common block does not contain 3D data'
  1507. dims = s[1:3]
  1508. d1 = dims-1
  1509.  
  1510. sl.p0cube = [[dims/4], [3 * dims/4]]
  1511. for i=0,7 do sl.p0[*,i] = $        ;Data coords of corners
  1512.     [ (i and 1) * d1[0], (i and 2)/2 * d1[1], (i and 4)/4 * d1[2]]
  1513.  
  1514. sl.orthop = [ 0., 0., 1., -dims[2]/2.]    ;Initial orthogonal plane
  1515.  
  1516. if n_elements(range) ge 2 THEN BEGIN    ;Range specified?
  1517.     sl.amax = range[1]
  1518.     sl.amin = range[0]
  1519. ENDIF ELSE BEGIN
  1520.     sl.amax = max(a, min = q)
  1521.     sl.amin = q
  1522. ENDELSE
  1523.  
  1524. old_slice = 0
  1525. az = 0.0
  1526. el = 0.0
  1527. z0 = [0.0, 0.0, 0.0]
  1528. d0 = slicer_plane_int()
  1529.  
  1530. sl.base = WIDGET_BASE(TITLE='IDL Slicer', /ROW)
  1531. ; Setting the managed attribute indicates our intention to put this app
  1532. ; under the control of XMANAGER, and prevents our draw widgets from
  1533. ; becoming candidates for becoming the default window on WSET, -1. XMANAGER
  1534. ; sets this, but doing it here prevents our own WSETs at startup from
  1535. ; having that problem.
  1536. WIDGET_CONTROL, /MANAGED, sl.base
  1537.  
  1538. lbase = WIDGET_BASE(sl.base, /COLUMN)
  1539. if keyword_set(detached) THEN BEGIN
  1540.     rbase = WIDGET_BASE(Title='Slicer', EVENT_PRO='SLICER_EVENT')
  1541.     sl.rbase = rbase
  1542. endif else rbase = WIDGET_BASE(sl.base)
  1543.  
  1544.  
  1545. sl.obuttons = WIDGET_BASE(rbase, /ROW)
  1546. junk = WIDGET_BASE(sl.obuttons, /exclusive, /row)
  1547. junk1 = WIDGET_BUTTON(junk, VALUE='Azimuth', UVALUE='AZIM')
  1548. junk1 = WIDGET_BUTTON(junk, VALUE='Elevation', UVALUE='ELEV')
  1549. WIDGET_CONTROL, junk1, /SET_BUTTON
  1550. junk1 = WIDGET_BUTTON(sl.obuttons, VALUE = 'Go', UVALUE='GOOBL')
  1551. WIDGET_CONTROL, sl.obuttons, MAP=0   ;Remove buttons for oblique mode
  1552.  
  1553. sl.draw = WIDGET_DRAW(rbase, XSIZE=resolution[0], YSIZE=resolution[1],$
  1554.     RETAIN=2, /BUTTON_EVENTS, /MOTION)
  1555.  
  1556. junk = WIDGET_BASE(lbase, COLUMN=3)
  1557. junk1 = WIDGET_BUTTON(junk, value="Done", uvalue = "EXIT", /NO_REL)
  1558. junk1 = WIDGET_BUTTON(junk, value="Erase", uvalue = "ERASE", /NO_REL)
  1559. junk1 = WIDGET_BUTTON(junk, value="Undo", uvalue = "UNDO", /NO_REL)
  1560. junk1 = WIDGET_BUTTON(junk, value="Help", uvalue = "HELP", /NO_REL)
  1561. junk1 = WIDGET_BUTTON(junk, VALUE='Orientation',/MENU)
  1562. ori_names = [ 'X Y Exchange', 'X Z Exchange', 'Y Z Exchange',$
  1563.     'X Reverse','Y Reverse','Z Reverse', 'Reset']
  1564. for i=0,6 do sl.ori_butt[i] = WIDGET_BUTTON(junk1, VALUE=ori_names[i],$
  1565.         UVALUE = 'ORIENTATION')
  1566. widget_control, sl.ori_butt[0], SET_BUTTON=1
  1567.  
  1568. junk1 = WIDGET_BUTTON(junk, VALUE='Interpolation',/MENU)
  1569. junk2 = WIDGET_BUTTON(junk1, VALUE='Off', UVALUE='INTERP0')
  1570. junk3 = WIDGET_BUTTON(junk1, VALUE='On', UVALUE='INTERP1')
  1571. WIDGET_CONTROL, junk3, SENS=0        ;Its on now.
  1572. widget_control, junk1, set_uvalue=[junk2, junk3]
  1573.  
  1574. junk1 = WIDGET_BASE(lbase, /FRAME, COLUMN=3, /EXCLUSIVE)
  1575.  
  1576. for i=0,nmodes-1 do $    ; Mode buttons
  1577.     junk2 = WIDGET_BUTTON(junk1, value=sl.mode_names[i], $
  1578.         uvalue=sl.mode_names[i], /NO_RELEASE)
  1579.  
  1580. junk = WIDGET_BASE(lbase, /FRAME, /COLUMN)
  1581. mode_base = WIDGET_BASE(junk)        ;For the mode dependent bases
  1582.  
  1583. for i=0,nmodes-1 do $
  1584.    if i ne 2 then sl.mode_bases[i] = WIDGET_BASE(mode_base, uvalue=0L, /COLUMN)
  1585.  
  1586.  
  1587. parent = sl.mode_bases[0]        ; slices mode
  1588. junk = WIDGET_DRAW(parent, XSIZE = sl_width, $
  1589.     YSIZE = sl_width * float(resolution[1]) / resolution[0])
  1590. WIDGET_CONTROL, parent, SET_UVALUE= junk
  1591.  
  1592. junk2 = WIDGET_BASE(parent, /ROW)
  1593. junk3 = WIDGET_BASE(junk2, /EXCLUSIVE, /ROW)
  1594. sl.draw_butt[0] = $
  1595.     WIDGET_BUTTON(junk3, VALUE = 'Draw', UVALUE='EXPOSE0', /NO_REL)
  1596. sl.draw_butt[1] = $
  1597.     WIDGET_BUTTON(junk3, VALUE = 'Expose', UVALUE='EXPOSE1', /NO_REL)
  1598. junk3 = WIDGET_BASE(junk2, /EXCLUSIVE, /ROW)
  1599. sl.draw_butt[2] = $
  1600.     WIDGET_BUTTON(junk3, VALUE = 'Orthogonal', UVALUE='ORTHO1', /NO_REL)
  1601. sl.draw_butt[3] = $
  1602.     WIDGET_BUTTON(junk3, VALUE = 'Oblique', UVALUE='ORTHO0', /NO_REL)
  1603.  
  1604. WIDGET_CONTROL, sl.draw_butt[0], /SET_BUTTON
  1605. WIDGET_CONTROL, sl.draw_butt[2], /SET_BUTTON
  1606.  
  1607. parent = sl.mode_bases[1]        ;Cube & Cut modes
  1608. junk = WIDGET_BASE(parent, /ROW)
  1609. junk1 = WIDGET_BUTTON(junk, value=' GO ', uvalue='GOCUBE', /NO_RELEASE)
  1610. junk1 = WIDGET_BUTTON(junk, value=' Cancel ', uvalue='CANCUBE', /NO_REL)
  1611. junk1 = WIDGET_BASE(junk, /EXCLUSIVE, /ROW)
  1612. junk = WIDGET_BUTTON(junk1, VALUE="Cut Into", UVALUE="CUTINTO", /NO_REL)
  1613. junk = WIDGET_BUTTON(junk1, VALUE="Cut Over", UVALUE="CUTOVER", /NO_REL)
  1614. junk = WIDGET_DRAW(parent, XSIZE = sl_width, $
  1615.     YSIZE = sl_width * float(resolution[1]) / resolution[0])
  1616. widget_control, parent, set_uvalue= junk
  1617.  
  1618. sl.mode_bases[2] = sl.mode_bases[1]    ;Cut is copy of cube
  1619.  
  1620. parent = sl.mode_bases[3]          ; Isosurface mode
  1621. junk = widget_button(parent, value='GO', UVALUE='GO')
  1622. junk = widget_base(parent, /row)
  1623. junk1 = widget_label(junk, value='Display: ')
  1624. junk = widget_base(junk, /row, /exclusive)
  1625. junk1 = widget_button(junk, value='High Side', uvalue='HIGH', /NO_REL)
  1626. junk1 = widget_button(junk, value='Low Side', uvalue='LOW', /NO_REL)
  1627. widget_control, junk1, /set_button    ;Set low value
  1628. sl.isop.slider = WIDGET_SLIDER(parent, xsize=sl_width, MINIMUM = 0, $
  1629.         UVALUE = "ISOSLIDE", $
  1630.         TITLE = 'Isosurface Threshold (%)', $
  1631.         MAXIMUM = 100)
  1632. isodraw = WIDGET_DRAW(parent, XSIZE=sl_width, YSIZE = 100, /BUTTON_EVENTS)
  1633.  
  1634. ;    Color tables
  1635. parent = sl.mode_bases[5]
  1636. junk1 = widget_base(parent, /ROW)
  1637. junk = WIDGET_BUTTON(junk1, VALUE = 'Color Tables', /MENU)
  1638. junk2 = 0
  1639. loadct, get_names = junk2
  1640. n = n_elements(junk2) < 24        ;# of buttons to make
  1641. FOR i = 0, n-1 DO sl.color_button[i] = $    ;Make color pull down buttons
  1642.     WIDGET_BUTTON(junk, VALUE=STRTRIM(junk2[i],2), uvalue='COLORS')
  1643.  
  1644. sl.cslide[0] = WIDGET_SLIDER(parent, xsize = sl_width, MINIMUM=0, /DRAG, $
  1645.     MAXIMUM=100, UVALUE = "STMIN", Title="Contrast Minimum", VALUE=0)
  1646. sl.cslide[1] = WIDGET_SLIDER(parent, xsize = sl_width, MINIMUM=0, /DRAG, $
  1647.     MAXIMUM=100, UVALUE = "STMAX", Title="Contrast Maximum", VALUE=100)
  1648. sl.cslide[2] = WIDGET_SLIDER(parent, xsize = sl_width, MINIMUM=0, /DRAG, $
  1649.     MAXIMUM=100, UVALUE = "SHADING", Title="Differential Shading (%)", $
  1650.     VALUE=20)
  1651.  
  1652.  
  1653. parent = sl.mode_bases[6]        ;Rotations mode
  1654. sl.rslide[0] = WIDGET_SLIDER(parent, xsize=sl_width, MINIMUM=-90, MAXIMUM=90, $
  1655.     UVALUE = "XROTATION", Title="X Axis Rotation", VALUE=30)
  1656. sl.rslide[1] = WIDGET_SLIDER(parent, xsize=sl_width, MINIMUM=-179, $
  1657.     MAXIMUM=179, UVALUE = "ZROTATION", Title="Z Axis Rotation", VALUE=30)
  1658. junk = WIDGET_BASE(parent, /frame, /row)
  1659. junk1 = WIDGET_LABEL(junk, VALUE='Z Aspect Ratio:')
  1660. sl.rslide[2] = WIDGET_TEXT(junk, VALUE='1.0     ', /EDIT, YSIZE=1, XSIZE=10)
  1661.  
  1662.  
  1663. parent = sl.mode_bases[7]        ;Journal mode
  1664. junk = WIDGET_BASE(parent, /COLUMN)
  1665. junk1 = WIDGET_BUTTON(junk, VALUE='Start Recording', UVALUE='RECORD', /NO_REL)
  1666. junk1 = WIDGET_BUTTON(junk, VALUE='Stop Recording', UVALUE='RECORDOFF',$
  1667.         /NO_REL)
  1668. junk1 = WIDGET_BUTTON(junk, VALUE='Playback', UVALUE='PLAYBACK', /NO_REL)
  1669. junk = WIDGET_BASE(parent, /ROW)
  1670. junk1 = WIDGET_LABEL(junk, value='File Name:')
  1671. sl.file_text[0] = WIDGET_TEXT(junk, xsize=24, ysize=1, $
  1672.     value='slicer.jou'+string(replicate(32b,14)), /EDIT, /FRAME)
  1673. sl.file_text[1] = WIDGET_TEXT(parent, xsize=32, ysize=1, $
  1674.     value='Journal Closed', /FRAME)
  1675.  
  1676. ;    Transparency buttons / slider
  1677. junk = WIDGET_BASE(lbase, /FRAME, /COLUMN)
  1678. sl.threshold_slider = WIDGET_SLIDER(junk, xsize=sl_width, $
  1679.     MINIMUM=0, MAXIMUM=100,$
  1680.     UVALUE="THRESHOLD", TITLE="Transparency Threshold (%)", VALUE=0)
  1681.  
  1682. junk1 = WIDGET_BASE(lbase, /FRAME)    ;Message base
  1683. sl.pos_text = WIDGET_TEXT(junk1, xsize=40, ysize=1)
  1684.  
  1685. ; Unmap mode dependent widgets  (Leave journal mapped because of obscure bug)
  1686. for i=1, nmodes-1 do widget_control, sl.mode_bases[i], MAP=0
  1687.  
  1688. WIDGET_CONTROL, sl.base, /REALIZE
  1689. if sl.rbase ne 0 then WIDGET_CONTROL, sl.rbase, /REALIZE
  1690. DEVICE, SET_GRAPHICS=3        ;Ensure copy graphics mode
  1691.  
  1692. WIDGET_CONTROL, sl.draw, get_value = junk
  1693. sl.window = junk        ;Main window
  1694. WIDGET_CONTROL, isodraw, get_value = junk
  1695. sl.isop.window = junk        ;Isosurface drawable
  1696. sl.isop.drawable = isodraw
  1697.  
  1698. sl.nc1 = (!d.n_colors < 256) -1 ;Colors we can use
  1699. sl.nc3 = (sl.nc1-3)/3        ;Colors per orientation
  1700.  
  1701. slicer_orientation,6        ;Reset to default orientation, erase
  1702. slicer_colors, 0
  1703.  
  1704. if n_elements(commands) gt 0 then slicer_playback, commands  ;Execute cmds?
  1705. if n_elements(cmd_file) gt 0 then slicer_playback, file = cmd_file
  1706.  
  1707. device,    TRANSLATION = tbl    ;Read hdw translation table
  1708.                 ;Distance between white and black
  1709. if !d.name eq 'X' then sl.xcol = tbl[0] xor tbl[sl.nc1]  $
  1710. else sl.xcol = 196        ;Windows.
  1711.  
  1712. tbl=0                ;Kill it
  1713. WSET, swin
  1714. XManager, "slicer", sl.base, EVENT_HANDLER = slicer_events, GROUP = group, $
  1715. /NO_BLOCK, MODAL=KEYWORD_SET(modal)
  1716. end
  1717.